home *** CD-ROM | disk | FTP | other *** search
- ;[*************************************************************************]
- ;[*************************************************************************]
- ;[* *]
- ;[* *]
- ;[* *]
- ;[* Copyright (C) 1991 by Borland International *]
- ;[* All rights reserved *]
- ;[* *]
- ;[* Written by Jeffrey J. Peters *]
- ;[* *]
- ;[* --------------------------------------------------------------- *]
- ;[* *]
- ;[* *]
- ;[* *]
- ;[* *]
- ;[*************************************************************************]
- ;[*************************************************************************]
- ;
-
- .186
- JUMPS
- LOCALS
-
- PRGNAME EQU 'Shellx'
- VER EQU '0.50'
-
-
- ;------------------------------
- ; Some Macros for this program
- ;------------------------------
- mDefISR MACRO i0,i1,i2,i3,i4,i5,i6,i7,i8,i9,iA; Allow for 10 interrupts
- IFNB <iA>
- Error <Too many arguments in call to mDefISR>
- ENDIF
- ISRTable label WORD ; Label to beginning of Table
- IRP iNum,<i0,i1,i2,i3,i4,i5,i6,i7,i8,i9>
- IFB <iNum> ; End of list of arguments ?
- ISRCount EQU (($ - OFFSET ISRTable) SHR 2)
- exitm
- ELSE
- Old&&iNum label dword ; Dword label to Old ISR
- OldISR&&iNum dw 2 dup (?); Old ISR Address
-
- ENDIF
- ENDM
- ENDM
- mGetISR MACRO iseg, i0,i1,i2,i3,i4,i5,i6,i7,i8,i9 ; Allow for 10 interrupts
- mov ah, 35h ; GetVect Function (INT 21h)
- IRP iNum,<i0,i1,i2,i3,i4,i5,i6,i7,i8,i9>
- IFB <iNum> ; End of list of arguments ?
- exitm
- ELSE
- .RADIX 16 ;Use Hexadecimal - Macro ;
- mov al, &&iNum ; Load the ISR number in AL
- .RADIX 10 ;Restore Radix to Base 10;
- int 21h ; Call INT 21h (DOS)
- mov &iseg:OldISR&&iNum, bx; Save ISR's Offset
- mov &iseg:OldISR&&iNum[2], es; Save Segment
- ENDIF
- ENDM
- ENDM
- mSetISR MACRO iseg,i0,i1,i2,i3,i4,i5,i6,i7,i8,i9 ; Allow for 10 interrupts
- mov ah, 25h ; GetVect Function (INT 21h)
- IRP iNum,<i0,i1,i2,i3,i4,i5,i6,i7,i8,i9>
- IFB <iNum> ; End of list of arguments ?
- exitm
- ELSE
- .RADIX 16 ;Use Hexadecimal - Macro ;
- mov al, &&iNum ; Load the ISR number in AL
- .RADIX 10 ;Restore Radix to Base 10;
- lea dx, &iseg:NewISR&&iNum; Point DS:DX to our ISR
- int 21h ; Call INT 21h (DOS)
- ENDIF
- ENDM
- ENDM
- mRestoreISR MACRO i0,i1,i2,i3,i4,i5,i6,i7,i8,i9
- mov ah, 25h ; GetVect Function (INT 21h)
- push ds
- IRP iNum,<i0,i1,i2,i3,i4,i5,i6,i7,i8,i9>
- IFB <iNum> ; End of list of arguments ?
- exitm
- ELSE
- .RADIX 16 ;Use Hexadecimal - Macro ;
- mov al, &&iNum ; Load the ISR number in AL
- .RADIX 10 ;Restore Radix to Base 10;
- lds dx, cs:Old&&iNum; Point DS:DX to our ISR
- int 21h ; Call INT 21h (DOS)
- ENDIF
- ENDM
- pop ds
- ENDM
- ;...................................
- mPutsz macro str
- ;
- ; Writes out a NULL terminated string to screen
- ;
-
-
- LOCAL again, first
- mov si, offset str
- jmp first
-
- again:
- int 29h ; undocumented 'screen write' DOS function
- first:
- lodsb
- or al, al
- jnz again
- endm
- ;...................................
-
- mPuts macro str
- ;
- ; Writes out a '$' terminated string to the screen
- ;
- mov dx, offset str
- mov ah, 9
- int 21h
- endm
- ;-------------------------
- TSR_STACKSIZE EQU 140 ; Stack size for the TSR
- MY_ID EQU 0EAh
- DETECT_CMD EQU 000h
- UNLOAD_CMD EQU 010h
-
-
- _TEXT SEGMENT PARA PUBLIC 'CODE' USE16
- ASSUME CS:_TEXT
- ASSUME DS:_TEXT
- ORG 0100h
- Begin: jmp Start
- TSRStack db TSR_STACKSIZE dup (?) ; TSR's stack space
- EndTSRStack dw ? ; End of TSR stack space
- _8stack db TSR_STACKSIZE + 20 dup (?) ; int 8 stack
- _8stacksize dw ?
- _8ss dw ?
- _8sp dw ?
- PrevSS dw ? ; Foreground's Stack Segment
- PrevSP dw ? ; Foreground's Stack Pointer
- PrevPSP dw ? ; Foreground's PSP
- TSRPSP dw ? ; The TSR's PSP
- mDefISR 2F,8,9 ; define old vect pointers
- ; This defines OLDxx as the old vector to be used in calls, jmp's and
- ; by the mGetISR, and mSetISR macros.
-
- _2F_flag db 0
-
- res_table LABEL BYTE ;------------------------------------------------;
- ; This is the table of memory that can be copied ;
- ; to from the another copy with the -M switch ;
- ;------------------------------------------------;
-
- _08_flag db 0 ;
- _08_count db 1 ; current count for timer
- _08_max db 18 ;
-
- res_table_len EQU $ - res_table
-
- ;----------------------------------------------------------------------------
- NewISR8 proc far ; New ISR for Timer Interrupt
- jmp dword ptr cs:[Old8]
- NewISR8 endp ; End of INT8 ISR
- ;----------------------------------------------------------------------------
- NewISR9 proc far ; New ISR for Keyboard Int
- jmp dword ptr cs:[Old9]
- NewISR9 endp ; End of INT8 ISR
- ;----------------------------------------------------------------------------
- NewISR2F proc far ; New ISR for Mux. Int.
- cmp ah, MY_ID
- je do_mine
- jmp end2F
- do_mine:
- cmp al, DETECT_CMD
- je do_detect
- cmp al, UNLOAD_CMD
- je do_unload
- jmp end2F
-
- do_detect:
- mov al, -1
- mov bx, cs
- jmp end2F
-
- do_unload:
- mRestoreISR 2F,8,9 ; reset vectors
- mov bx, cs
- jmp end2F
-
- end2F:
- jmp dword ptr cs:[Old2F]
- NewISR2F endp ; End of INT2F ISR
- ;----------------------------------------------------------------------------
- ;[]=-=-=-=-=-=-=-=-=-=-=[ ACTUAL TSR ROUTINE...]=-=-=-=-=-=-=-=-=-=-=-=-=-=-[]
- ;| This is where control is passed when our TSR is activated... various |
- ;| things are done depending upon the requirements of the TSR.. It is |
- ;| advisable to save/restore the following: REGISTERS/STACK/PSP/DTA/XtError|
- ;[]=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=[]
- TSR proc near
- push ds ; Save current DS value
- push cs ; Set DS to the code segment
- pop ds ; DS -> code segment
- assume ds:_TEXT ; DS -> code segment
- mov PrevSS, ss ; Save Foreground SS
- mov PrevSP, sp ; Save Foreground SP
- cli ; Disable interrupts
- push cs ; Push CodeSeg on stack
- pop ss ; SS -> code segment
- mov sp, OFFSET EndTSRStack ; SP -> End of TSR Stack
- sti ; Reenable interrupts
- push ax ; Save AX register
- push bx ; Save BX register
- push cx ; Save CX register
- push dx ; Save DX register
- push si ; Save SI register
- push di ; Save DI register
- push es ; Save ES register
- mov ah, 62h ; Func 62: Get current PID
- int 21h ; Call MS DOS
- mov PrevPSP, bx ; Save the foreground's PSP
- mov ah, 50h ; Func 50: Set current PID
- mov bx, TSRPSP ; Load TSR's process ID
- int 21h ; Call MS DOS
-
- ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
-
- ;
- ; TSR code goes here
- ;
-
- message_end:
- ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
- EXIT_TSR:
- mov bx, cs:PrevPSP ; Restore the Foreground's PSP
- mov ah, 50h ; Set PIP: Function 50h
- int 21h ; Call MS DOS
- pop es ; Restore ES register
- pop di ; Restore DI register
- pop si ; Restore SI register
- pop dx ; Restore DX register
- pop cx ; Restore CX register
- pop bx ; Restore BX register
- pop ax ; Restore AX register
- cli ; Disable interrupts
- mov ss, cs:PrevSS ; Restore SS register
- mov sp, cs:PrevSP ; Restore SP register
- sti ; Reenable interrupts
- pop ds ; Restore DS value
- ret ; Return to Foreground
- TSR endp
- ; - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
-
- ;[]-=-=-=-=-=-=-=-=-=-[ TRANSIENT PORTION OF PROGRAM ]=-=-=-=-=-=-=-=-=-=-=-[]
- ;| This is the transient portion of the TSR... All Data and Code in the |
- ;| following section is discarded upon Residency... So put everything not |
- ;| needed in memory here... |
- ;[]-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-[]
- Transient:
- program db 'SHLX'
- version db VER,' '
-
- verbopt db 0
- modopt db 0
- XMSvect dd ?
- isXMS db 1
- loadhi db 0
- UMBseg dw 0
- XMSnone_s db 10,13,'No XMS present.',10,13,'$'
- XMSfree_s db 10,13,'Largest block avail. : '
- XMSfree db '0000 k',10,13,'$'
- XMSver_s db 10,13,'XMS detected, version: '
- XMSmajor db '00.'
- XMSminor db '00 HMA free: '
- XMShma db '0'
- db '$'
-
- EnvFreeFail db 10,13,'Unable to Free Environment Block',10,13,'$'
- title_s db PRGNAME,' v',VER,' Copyright (c) 1991 by Borland '
- db 'International',10,13,'$'
-
- v_id_s db 10,13,'Int-2F, using ID: '
- v_id_n db '00h, ','$'
- v_seg_s db "reports the resident copy's PSP is located at: "
- v_seg_n db '0000h',10,13,'$'
- v_2F_bad db 'cannot find any resident copy.',10,13,'$'
- modified_s db 'Resident copy has been updated',10,13,'$'
- loaded_s db 7,'ERROR: ',PRGNAME,' already resident, exiting...',10,13,'$'
- loaded_high_s db 'TSR is loaded high (UMB)',10,13,'$'
- unloaded_s db 'Unload: successful.',10,13,'$'
- no_unload_s db 7,'ERROR: Cannot Unload TSR at this time Code: '
- no_unload_s_d db '00',10,13,'$'
- UMBerror_s db 07,'ERROR: UMB error code:'
- UMBerror_num db '00 ',10,13,'$'
- not_loaded_s db 7,'ERROR: ',PRGNAME,' is not loaded at this time',10,13,'$'
- bad_version_s db 7,'ERROR: A copy with a different version was found',10,13,'$'
- wrong_option_s db 7,'ERROR: Unrecognized option.',10,13,'$'
- help_s db 'Usage: ',PRGNAME,' [-options] (xxxx means 4 hex digits)',10,10,13
- db '-V Verbose messages (default = no)',10,13
- db '-VV Inquire about resident copy (default = no)',10,13
- db '-X Print XMS information (for debugging only)',10,13
- db '-U Load high (UMB) (default = no)',10,13
- db '-R Removes the TSR from memory (either high or low)',10,13
- db '-?, -h Shows this help screen',10,13,'$'
-
- author_s db 10,13,"This program was written by Jeffrey J. Peters for Borland International's",10,13
- db 'technical support group. Those who contributed are:',10,10,13
- db ' Bruneau Babet',10,13
- db ' Shea Anderson',10,13
- db ' Greg MacDonald',10,13
- db 10,13,'$'
-
- Start:
- mov TSRPSP, es ; Save the TSR's PSP segment
- assume ds:_TEXT ; DS -> Code Segment
- mov bx, 02Ch ; offset of env. in psp
- mov es, cs:[bx] ; ES -> Environment Block
- mov ah, 49h ; Function 49h: Free Block
- int 21h ; Call MS DOS
- jnc do_the_cmd ; Error freeing EnvBlock
-
- mPuts EnvFreeFail ; Print Error Message
- jmp exit_bad
-
- do_the_cmd:
- mPuts title_s ; Print title string
- call GetXMSEntry
- jz @@@1
- mov cs:[isXMS], 0
-
- @@@1:
-
- mov ax, cs
- mov ds, ax
- mov es, ax
- mov di, 5
- mov si, offset version
- mov cx, 5
- rep movsb ; put version string in PSP
-
- call ParseCMD
- cmp cs:[modopt], 0
- je regular_check
-
- check_ver:
- call CheckInstalled
- jnz not_loaded
-
- mov ds, bx
- push cs
- pop es
- mov di, 5 ; offset into our PSP
- mov si, 5 ; offset into res's PSP
- mov cx, 5 ; number of bytes to compare
- repe cmpsb ; compare while they're equal
- jcxz modify_res
-
- push cs
- pop ds
- mPuts bad_version_s
- jmp exit_bad
-
- modify_res:
- push ds
- pop es
- push cs
- pop ds
- mov si, offset res_table
- mov di, offset res_table
- mov cx, res_table_len
- shr cx, 1
- rep movsw
- jnc $ + 3
- movsb
-
- modify_done:
- mPuts modified_s
- jmp exit_bad
-
- regular_check:
- cmp bp, 0
- je unload ; unload TSR
- je wrong_option
- cmp bp, 1
- je Help ; print help
- cmp bp, 2
- je wrong_option
- cmp bp, 4
- jae exit_bad ; Just exit
-
- ; 3 means install
-
- ; check via 2F, to see if already installed.
- call CheckInstalled ; ZF=1 -- installed
- jnz load_res
-
- already_in:
- mPuts loaded_s
- mov ax, 4c01h
- int 21h
-
- temp label word
- dw ?
-
- unload:
- call CheckInstalled ; bx gets TSR's PSP
- jnz not_loaded
-
- mov cs:[TSRPSP], bx ; save TSR's PSP
-
- xor ax, ax
- mov es, ax
- mov ax, bx
-
- mov cs:[temp], '08' ; test 8
-
- mov bx, 4 * 8h
- cmp es:2[bx], ax
- jne no_unload
-
- mov cs:[temp], '09' ; test 9
-
- mov bx, 4 * 9h
- cmp es:2[bx], ax
- jne no_unload
-
- mov cs:[temp], '2F' ; test 2F
-
- mov bx, 4 * 2fh
- cmp es:2[bx], ax
- jne no_unload
-
- call UnhookTSRvectors ; now that it's save, unhook
-
- ;
- ; Unload the resident TSR:
- ; We first set the current PSP to that of the TSR's
- ; then we modify the termination address of the TSR (PSP:[0Ah]) to point
- ; to our 'back_here' function in the transient copy.
- ;
- mov bx, offset back_here ; set terminate address
- mov es, cs:[TSRPSP]
- mov word ptr es:[0Ah], bx
- mov word ptr es:2[0Ah], cs
-
- push cs ; reset DS for us
- pop ds
- mPuts unloaded_s
-
- mov ah, 50h ; UNDOC Set PSP segment
- mov bx, cs:[TSRPSP] ; TSR PSP segment
- int 21h
-
- mov ax, 4C80h ; Terminate current (TSR) Process
- int 21h ; This jumps to back_here
-
- no_unload:
- mov bx, offset no_unload_s_d
- mov ax, cs:[temp]
- xchg al, ah
- mov word ptr cs:[bx], ax
-
- mPuts no_unload_s
- mov ax, 4C01h
- int 21h ; Exit with no unload message
-
- not_loaded:
- mPuts not_loaded_s
- mov ax, 4C04h
- int 21h
-
-
- back_here:
- mov ah, 50h ; now that we're back, restore our PSP
- mov bx, cs
- int 21h
-
- mov ax, cs:[TSRPSP]
- cmp ax, 0A000h
- jb finish_unload
- call FreeUMB
- jz ErrorInUMB
-
- finish_unload:
-
- mov ax, 4C00h
- int 21h ; Now exit for real.
-
- CheckInstalled proc near
- mov ax, 256 * MY_ID
- int 2Fh
- cmp al, -1
- ;
- ; ZF = 1 if we are already loaded else ZF = 0
- ;
-
- pushf
- cmp cs:[verbopt], 0
- je checkopt_done
-
- push bx
- mov ax, cs
- mov es, ax
- mov ax, MY_ID
- mov di, offset v_id_n
- call BCDwrite
- mPuts v_id_s
- pop bx
-
- popf
- pushf
- jnz __not_here
- push bx
- mov di, offset v_seg_n
- pop ax
- push ax
- xchg al, ah
- call BCDwrite
- pop ax
- call BCDwrite
- mPuts v_seg_s
-
- jmp checkopt_done
-
- __not_here:
- push bx
- mPuts v_2F_bad
- pop bx
-
- checkopt_done:
- popf
- ret
- CheckInstalled endp
-
- UnhookTSRvectors proc near
- mov ah, MY_ID
- mov al, UNLOAD_CMD
- int 2Fh
- ret
- UnhookTSRvectors endp
-
-
-
- ;-----------------------------------------------------------------------------
- ParseCMD proc near
- cld
- mov bx, 0081h
- push cs
- pop ds
- call near ptr _UpCase
-
-
- mov bp, 3 ; ret code for Install
- cmp byte ptr cs:[80h], 0
- je ParseEnd
- push cs
- pop ds
- mov si, 81h
- GetNext:
- lodsb
- cmp al, 13
- je ParseEnd
- cmp al, '-'
- je get_switch
- cmp al, '/'
- je get_switch
- cmp al, ' '
- je GetNext
-
- mov bp, 2
- jmp ParseEnd
-
-
- get_switch:
- lodsb
- cmp al, '?' ; help
- je ParseHelp
-
- or al, 60h ; convert to lower case
- cmp al, 'r'
- je ParseUnl
- cmp al, 'u'
- je GetLoadhiOption ; Load it high or not?
- cmp al, 'x'
- je GetXMSOption ; print out XMS info
- cmp al, 'v'
- je GetVerboseOption ; for verbose messages
- cmp al, 'i'
- je do_author ; Author screen
- cmp al, 'm'
- je GetModifyOption ; modify resident copy
- cmp al, 'h' ; help
- mov bp, 1
- je ParseEnd
- mov bp, 2 ; Wrong option
- ; 4 - Generic error
-
- ParseEnd:
- ret
- ParseCMD endp
- ;-----------------------------------------------------------------------------
- ParseUnl:
- mov bp, 0
- jmp ParseEnd
-
- ParseHelp: mov bp, 1
- jmp ParseEnd
-
- GetModifyOption:
- mov bp, 4
- lodsb
- mov cs:[modopt], 0
- cmp al, '-'
- je GetNext
- mov cs:[modopt], 1
- cmp al, ' '
- je GetNext
- cmp al, 0dh ; Last option
- je ParseEnd
- mov bp, 2 ; bad option
- jmp ParseEnd
-
- GetVerboseOption:
- lodsb
- mov cs:[verbopt], 0
- cmp al, '-'
- je GetNext
- mov cs:[verbopt], 1
- cmp al, ' '
- je GetNext
- cmp al, 'V'
- je do_now
- cmp al, 0dh ; Last option
- je ParseEnd
- mov bp, 2 ; bad option
- jmp ParseEnd
-
- do_now:
- mov cs:[verbopt], 1
- call CheckInstalled
- mov bp, 4
- jmp ParseEnd
-
-
- GetLoadhiOption:
- mov cs:[loadhi], 1
- mov bp, 3
- jmp ParseEnd
-
- GetXMSOption:
- call PrintXMSInfo
- mov bp, 4
- jmp ParseEnd
-
- do_author:
- mPuts author_s
- mov bp, 4
- jmp ParseEnd
-
- Help:
- mPuts help_s
-
- mov ax, 4C02h
- int 21h
-
- wrong_option:
- mPuts wrong_option_s
- mov ax, 4C03h
- int 21h
-
- load_res:
-
- test_hi_low:
- push cs
- pop ds
-
- cmp cs:[loadhi], 0
- je load_low
- mov cs:[loadhi], 0
- cmp cs:[isXMS], 1
- jne load_low
- mov cs:[loadhi], 1
-
- mov ax, offset Transient ; # of bytes to keep high
- shr ax, 4 ; convert to paragraphs
- call PutCodeInUMB
- jz ErrorInUMB
- mov ax, cs:[UMBseg]
-
- dec ax
- mov es, ax
- mov di, 8
- mov si, offset program
- mov cx, 8 /2
- rep movsw ; put prog name in UMB
-
- mov ds, cs:[UMBseg]
-
- load_low:
- mGetISR ds, 2F, 8, 9
- mSetISR ds, 2F, 8, 9
- push cs
- pop ds
-
- cmp cs:[loadhi], 1
- je exit_UMB
- mov dx, offset Transient
- int 27h ; go resident
-
-
- fix_al:
- sub al, 30h
- add al, 'A' - 10
- jmp do_UMB_error
-
- fix_ah:
- sub ah, 30h
- add ah, 'A' - 10
- jmp fix_ah_ret
-
- ErrorInUMB:
- mov ah, 0
- mov al, bl
- shl ax, 4
- mov al, bl
- and ax, 0F0Fh
- or ax, 3030h
- cmp ah, 39h
- ja fix_ah
- fix_ah_ret:
- cmp al, 39h
- ja fix_al
-
-
- do_UMB_error:
- push cs
- pop ds
- xchg al, ah
- mov word ptr cs:[UMBerror_num], ax
- mPuts UMBerror_s
- mov cs:[loadhi], 0
- jmp load_low
-
- exit_bad:
- mov ax, 4c01h
- int 21h
-
- exit_UMB:
- mPuts loaded_high_s
- mov ax, 4c00h
- int 21h
-
- ;- - - - - - - - - - - - - - - - - - -
- _UpCase:
- cmp byte ptr [bx], 0
- je @done_uc
- cmp byte ptr [bx], 13
- je @done_uc
- cmp byte ptr [bx], 'a'
- jb @redo_uc
- cmp byte ptr [bx], 'z'
- ja @redo_uc
- and byte ptr [bx], 0DFh ; lower to upper case
- @redo_uc:
- inc bx
- jmp _UpCase
- @done_uc:
- ret
- ;- - - - - - - - - - - - - - - - - - -
-
-
- ;----------------------------------------------------------------------------
- atoi proc near
- ;
- ; ax (ah:al) contains 2 ascii hex digits.
- ; returns the value in ax
- ; upon error, cf = 1
-
- clc
- xor bx, bx
- push ax
- call one_ch
- pop ax
- jc the_atoi_error
- mov dx, bx
- mov cl, 4
- shl dx, cl
- xchg al, ah
- xor bx, bx
- call one_ch
- jc the_atoi_error
- add dx, bx
- mov ax, dx
- jmp atoi_end
-
- one_ch:
- cmp al, '0'
- jb atoi_error
- cmp al, '9'
- ja letter
- mov bl, al
- sub bl, '0'
- jmp one_ch_end
-
- letter:
- cmp al, 'A'
- jb atoi_error
- cmp al, 'F'
- ja atoi_error
- mov bl, al
- sub bl, 'A' - 10
-
- one_ch_end:
- clc
- retn
-
- atoi_error:
- stc
- retn
-
- the_atoi_error:
- stc ; error condition
-
- atoi_end:
- ret
- atoi endp
- ;----------------------------------------------------------------------------
- ;----------------------------------------------------------------------------
- BCDwrite proc
- ; AL has two BCD digits that will be written to ES:DI in ASCII form
-
- mov ah, al
- and al, 0fh
- shr ah, 4
- ; ah has MSD
- ; al has LSD
- or ax, 3030h
- xchg al, ah
-
- cmp ah, 39h
- ja _fix_ah
- _fix_ah_ret:
- cmp al, 39h
- ja _fix_al
-
-
- write_it:
-
- stosw
- ret
-
- _fix_al:
- sub al, 30h
- add al, 'A' - 10
- jmp write_it
-
- _fix_ah:
- sub ah, 30h
- add ah, 'A' - 10
- jmp _fix_ah_ret
-
- BCDwrite endp
- ;---------------------------------------------------------------------------
-
- GetXMSEntry proc
- ;
- ; zf = 1 if no XMS is avail, else zf = 0
- ;
- mov ax, 4300h ; check if XMS is avail?
- int 2Fh
- cmp al, 80h
- jne endXMS
-
- mov ax, 4310h ; get entry point
- int 2Fh
- mov word ptr cs:[XMSvect], bx
- mov word ptr cs:2[XMSvect],es
- endXMS:
- ret
- GetXMSEntry endp
- ;----------------------------------------------------------------------------
- PrintXMSInfo proc
- ;
- ; Prints out the version info and HMA status for XMS
- ;
- cmp cs:[isXMS], 0
- jne p_xms_cont
- mPuts XMSnone_s
- ret
-
- p_xms_cont:
- mov ah, 0
- call cs:[XMSvect]
- push cs
- pop es
- push ax
- mov di, offset XMSmajor
- mov al, ah
- call BCDwrite
- pop ax
- mov di, offset XMSminor
- call BCDwrite
-
- mov ah, 07h
- call cs:[XMSvect]
- xor al, 1 ; invert it
- or al, 30h
- mov cs:[XMShma], al
- mPuts XMSver_s
-
- mov ah, 8
- call cs:[XMSvect]
- push ax
- mov di, offset XMSfree
- mov al, ah
- call BCDwrite
- pop ax
- mov di, offset XMSfree + 2
- call BCDwrite
-
- mPuts XMSfree_s
-
- ret
- PrintXMSInfo endp
- ;----------------------------------------------------------------------------
- PutCodeInUMB proc
- ;
- ; copies the code from low memory to UMB if availible
- ;
- ; call with:
- ; ax - containing the number of paragraphs to copy up to UMB
- ;
- ; returns:
- ; zf = 0 on success or
- ; zf = 1 on error
- ;
-
- inc ax
- mov dx, ax
- mov ah, 10h
- call cs:[XMSvect]
- cmp ax, 1
- je XMS_put_cont
- cmp ax, ax
- je XMSfail
-
- XMS_put_cont:
-
- mov cs:[UMBseg], bx
- mov si, 0
- mov di, 0
- push cs
- pop ds
- mov es, bx
- mov cx, dx
- shl cx, 3
- rep movsw ; copy code to UMB
-
- XMSfail:
- ret
- PutCodeInUMB endp
- ;----------------------------------------------------------------------------
- FreeUMB proc
- ;
- ; Frees the UMB segment given
- ;
- ; call with:
- ; ax - segment base of UMB
- ;
- ; returns:
- ; zf = 0 on success or
- ; zf = 1 on error
- ;
- mov dx, ax
- mov ah, 11h
- call cs:[XMSvect]
- cmp ax, 0
- FreeUMBend:
- ret
- FreeUMB endp
- ;----------------------------------------------------------------------------
- ;----------------------------------------------------------------------------
-
- _TEXT ENDS
- END Begin
-
-